home *** CD-ROM | disk | FTP | other *** search
/ Libris Britannia 4 / science library(b).zip / science library(b) / DDJMAG / DDJ9005.ZIP / AYERS.ZIP / MRKTSMLT.CLS < prev    next >
Text File  |  1990-02-26  |  5KB  |  172 lines

  1.  
  2. Object subclass: #MarketSimulator
  3.   instanceVariableNames: 
  4.     'running notify counters frame statusFrame totalCustomers startTime '
  5.   classVariableNames: 
  6.     'MaxTime MaxCounters MinTime '
  7.   poolDictionaries: '' !
  8.  
  9. !MarketSimulator class methods !
  10.  
  11. new
  12.     MaxCounters := 3.  MinTime := 1.  MaxTime := 15.
  13.     ^super new initialize.!
  14.  
  15. priority
  16.     ^2.! !
  17.  
  18.  
  19. !MarketSimulator methods !
  20.  
  21. elapsedTime
  22.     |time field offset|
  23.     time := Time now subtractTime:startTime.
  24.     field := 'ELAPSED TIME ', time printString.
  25.     offset := statusFrame center x
  26.                 - ((SysFont stringWidth:field) // 2).
  27.     field displayAt:statusFrame origin + (offset @ 0).!
  28.  
  29. initialize
  30.     totalCustomers := 0.
  31.     running := false.!
  32.  
  33. newCustomer
  34.     |counter customer|
  35.     (counter := self shortestLine) isNil
  36.         ifFalse:[
  37.             customer := Customer new
  38.                 counter:counter;
  39.                 position:counter endOfLinePosition;
  40.                 display;
  41.                 start;
  42.                 yourself.
  43.             totalCustomers := totalCustomers + 1.
  44.             ('CUSTOMERS SERVED:', totalCustomers printString)
  45.                 displayAt:statusFrame origin.
  46.             self send:#addCustomer to:counter with:customer].!
  47.  
  48. reframe:aFrame
  49.     |statusHeight w h maxCounters maxCustomers x y|
  50.     CursorManager execute change.
  51.     frame := aFrame.
  52.     statusHeight := SysFont height + 4.
  53.     statusFrame := aFrame origin + (2 @ 2)
  54.                         extent:(aFrame width - 4) @ statusHeight.
  55.     w := CheckoutCounter width + Customer width + 2.
  56.     h := CheckoutCounter height + Customer height + 4.
  57.     maxCounters := ((aFrame width - Customer width) // w)
  58.                         min:MaxCounters.
  59.     maxCustomers := ((aFrame height - statusHeight - h)
  60.                         // Customer height)
  61.                             min:CheckoutCounter maxCustomers.
  62.     x  := aFrame origin x
  63.             + ((aFrame width - (maxCounters * w)) // 2)
  64.             + Customer width.
  65.     y  := aFrame corner y - h.
  66.     CheckoutCounter maxCustomers:maxCustomers.
  67.     counters := Array new:maxCounters.
  68.     1 to:maxCounters do:[:i|
  69.         counters
  70.             at:i
  71.             put:(CheckoutCounter new
  72.                     position:x @ y;
  73.                     display;
  74.                     yourself).
  75.         x := x + w].
  76.     CursorManager normal change.!
  77.  
  78. release
  79.     1 to:counters size do:[:i|
  80.         (counters at:i) release.
  81.         counters at:i put:nil].
  82.     counters release.
  83.     counters := nil.
  84.     notify := nil.
  85.     super release.!
  86.  
  87. run
  88.     self newCustomer.
  89.     [running]
  90.         whileTrue:[
  91.             self sleep:(RandomNumber from:MinTime to:MaxTime).
  92.             running ifTrue:[self newCustomer]].
  93.     self shutdown.
  94.     (notify isKindOf:Semaphore)
  95.         ifTrue:[notify signal].!
  96.  
  97. running   
  98.     ^running.!
  99.  
  100. send:aMessage to:anObject 
  101.     self send:aMessage to:anObject with:nil.!
  102.  
  103. send:aMessage to:anObject with:anArgument
  104.     |queue|
  105.     (queue := anObject messageQueue) isNil
  106.         ifFalse:[
  107.             queue send:aMessage.
  108.             anArgument isNil ifFalse:[queue send:anArgument]].
  109.     Processor yield.!
  110.  
  111. shortestLine 
  112.     |fewest length shortest| 
  113.     fewest := 9999. 
  114.     1 to:counters size do:[:i| 
  115.         (length := (counters at:i) length) < fewest 
  116.             ifTrue:[ 
  117.                 fewest := length. 
  118.                 shortest := i]]. 
  119.     fewest < CheckoutCounter maxCustomers 
  120.         ifTrue:[^counters at:shortest] 
  121.         ifFalse:[^nil].!
  122.  
  123. shutdown
  124.     |semaphore|
  125.     semaphore := Semaphore new.
  126.     counters do:[:aCounter|
  127.         aCounter isNil
  128.             ifFalse:[
  129.                 aCounter stop:semaphore.
  130.                 semaphore wait]].!
  131.  
  132. sleep:numberOfSeconds
  133.     |timeout lastTime time|
  134.     timeout := Time now asSeconds + numberOfSeconds.
  135.     lastTime := 0.
  136.     [running and:[(time := Time now asSeconds) < timeout]]
  137.         whileTrue:[
  138.             time = lastTime
  139.                 ifFalse:[
  140.                     self
  141.                         timeRemaining:(timeout - time);
  142.                         elapsedTime.
  143.                     lastTime := time].
  144.             Processor yield].!
  145.  
  146. start
  147.     counters do:[:aCounter|
  148.         aCounter isNil ifFalse:[aCounter start]].
  149.     running
  150.         ifFalse:[
  151.             startTime := Time now.
  152.             running := true.
  153.             [self run] forkAt:self class priority].!
  154.  
  155. stop:notifySemaphore 
  156.     running 
  157.         ifTrue:[ 
  158.             notify := notifySemaphore. 
  159.             running := false] 
  160.         ifFalse:[ 
  161.             self shutdown. 
  162.             notifySemaphore signal].!
  163.  
  164. timeRemaining:seconds
  165.     |fieldWidth field offset|
  166.     fieldWidth := 3.
  167.     field := 'NEXT CUSTOMER:',
  168.                 (seconds printString flushedRightIn:fieldWidth).
  169.     offset := statusFrame width
  170.                 - (SysFont stringWidth:field).
  171.     field displayAt:statusFrame origin + (offset @ 0).! !
  172.